ExportGridIntegerToESRI_ASCII Subroutine

private subroutine ExportGridIntegerToESRI_ASCII(layer, fileName)

Uses

export grid_integer to a ESRI ASCII file.

Arguments

Type IntentOptional Attributes Name
type(grid_integer), intent(in) :: layer
character(len=*), intent(in) :: fileName

Variables

Type Visibility Attributes Name Initial
integer(kind=short), public :: fileUnit
integer(kind=short), public :: i
integer(kind=short), public :: ios
integer(kind=short), public :: j

Source Code

SUBROUTINE ExportGridIntegerToESRI_ASCII &
!
(layer, fileName) 

USE Utilities, ONLY: &
!Imported routines:
GetUnit

IMPLICIT NONE

!Arguments with intent(in):
TYPE (grid_integer), INTENT (IN) :: layer
CHARACTER (LEN = *), INTENT (IN) :: fileName

!Local variables:
INTEGER (KIND = short)          :: fileUnit
INTEGER (KIND = short)          :: ios
INTEGER (KIND = short)          :: i,j
!------------end of declaration------------------------------------------------

!open file
fileUnit = GetUnit ()
OPEN (UNIT = fileUnit, file = fileName, IOSTAT = ios)
IF (ios /= 0) THEN
  CALL Catch ('error', 'GridLib',        &
              'error opening file: ',    &
              code = openFileError, argument = fileName )
END IF

!write header
WRITE(fileUnit,'(a14,i4)')    "ncols         ", layer % jdim
WRITE(fileUnit,'(a14,i4)')    "nrows         ", layer % idim
WRITE(fileUnit,'(a14,f15.5)') "xllcorner     ", layer % xllcorner
WRITE(fileUnit,'(a14,f15.5)') "yllcorner     ", layer % yllcorner
WRITE(fileUnit,'(a14,f15.5)') "cellsize      ", layer % cellsize
WRITE(fileUnit,'(a14,i8)')    "NODATA_value  ", layer % nodata

!write data
DO i = 1,layer % idim 
   DO j = 1, layer % jdim - 1
      WRITE(fileUnit,'(i8," ")', ADVANCE = 'no') layer % mat(i,j)
   END DO
   WRITE(fileUnit,'(i8," ")') layer % mat(i,layer % jdim)
END DO 

CLOSE (fileUnit)

END SUBROUTINE ExportGridIntegerToESRI_ASCII